ETinit Subroutine

public subroutine ETinit(inifile, time)

Initialize evapotranspiration computation

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inifile
type(DateTime), intent(in) :: time

Variables

Type Visibility Attributes Name Initial
type(IniList), public :: etini
integer(kind=short), public :: i
integer(kind=short), public :: j

Source Code

SUBROUTINE ETinit &
!
( inifile, time )

IMPLICIT NONE

!Arguments with intent(in):
CHARACTER (LEN = *), INTENT(IN) :: inifile
TYPE (DateTime), INTENT(IN) :: time

!local declarations:
TYPE (IniList) :: etini
INTEGER (KIND = short) :: i, j

!------------------------------end of declarations-----------------------------

!open and read configuration file
CALL IniOpen (inifile, etini)

!dt
IF (KeyIsPresent('dt', etini) ) THEN	
   dtET = IniReadInt ('dt', etini)
ELSE
    CALL Catch ('error', 'Evapotranspiration',   &
                'dt missing in configuration file' )
END IF

!initialize PET map
CALL NewGrid (pet, mask)
CALL NewGrid (pe, mask)
CALL NewGrid (pt, mask)


!model assignment method
IF (KeyIsPresent('model-assignment', etini ) ) THEN
    model_assignment = IniReadInt ('model-assignment', etini)
ELSE
   CALL Catch ('error', 'Evapotranspiration',   &
            'model-assignment missing in configuration file')
END IF   

!set model
IF (model_assignment == 1) THEN

    model = IniReadInt ('model', etini )
    
    CALL NewGrid (model_map, mask)
    
    CALL CheckSpecificProperties (model, etini)
    
    model_map = model
  
ELSE 
    model = -1
    
    !check map is present
    IF ( .NOT. SectionIsPresent ('model-map', etini) ) THEN
         CALL Catch ('error', 'Evapotranspiration',   &
            'model-map missing in configuration file')
    END IF
    
    !read map
    CALL GridByIni (etini, model_map, 'model-map')
    
    IF ( .NOT. CRSisEqual (mask, model_map, .TRUE.) ) THEN
        CALL Catch ('error', 'Evapotranspiration',   &
            'something seems wrong in model-map')
    END IF
    
    !scan for et models
    model_vector = -1
    DO i = 1, model_map % idim
        DO j = 1, model_map % jdim
            IF (model_map % mat(i,j) /= model_map % nodata) THEN
                model_vector (model_map % mat (i,j)) = model_map % mat (i,j)
            END IF
        END DO
    END DO

    DO i = 1, ET_MODELS
         CALL CheckSpecificProperties (model_vector (i), etini)
    END DO

END IF

!crop coefficient
IF ( KeyIsPresent ('use-crop-coefficient', etini) ) THEN
    IF (IniReadInt ('use-crop-coefficient', etini) == 1 ) THEN
        useCropCoefficient = .TRUE.
    END IF
END IF

IF (useCropCoefficient) THEN
    IF ( .NOT. SectionIsPresent ('crop-coefficient', etini) ) THEN
        CALL Catch ('error', 'Evapotranspiration',   &
                'crop-coefficient section is missing in configuration file' )
    END IF
    
    !allocate map
    CALL NewGrid (kc_map, mask)
    
    !file
    filenameKc = IniReadString ('file', etini, section = 'crop-coefficient')
    
    !interpolation method
    interpolationMethodKc = IniReadInt ('interpolation', etini, section = 'crop-coefficient')
    
    IF (interpolationMethodKc == 0) THEN !data are stored in net-cdf file
       IF ( KeyIsPresent ('variable', etini, section = 'crop-coefficient') ) THEN
          kc_map % var_name = IniReadString ('variable', etini, section = 'crop-coefficient')
       ELSE IF  (KeyIsPresent ('standard_name', etini, section = 'crop-coefficient') ) THEN
          kc_map % standard_name = IniReadString ('standard_name', etini, section = 'crop-coefficient')
       ELSE
          CALL Catch ('error', 'Evapotranspiration',   &
		       'standard_name or variable missing in section crop-coefficient' )
       END IF
       
       !Get the dt of imported  field. Assume dt is regular	
       dtKc = GetDtGrid (filenameKc, .TRUE.)
       
    ELSE !open file containing local measurements
       fileunitKc = GetUnit ()
	   OPEN ( fileunitKc, file = filenameKc (1:LEN_TRIM(filenameKc)), status = 'old')
       
       !populate  metadata
       CALL ReadMetadata (fileunitKc, kc_stations)
       
       !set dt
       dtKc = kc_stations % timeIncrement
        
       !read map of crop coefficient code
       CALL GridByIni (ini = etini, grid = kc_code_map, &
                section = 'crop-coefficient', subsection = 'code-map')  
    END IF
    
    !set time
    tnewKc = time
    
END IF

!set time
tnewET = time


!  Configuration terminated. Deallocate ini database
CALL IniClose (etini)  

RETURN
END SUBROUTINE ETinit